perm filename GRNFUN.SAI[S,HE] blob sn#688234 filedate 1982-11-22 generic text, type C, neo UTF8
COMMENT ⊗   VALID 00009 PAGES
C REC  PAGE   DESCRIPTION
C00001 00001
C00003 00002	ENTRY GrnLine, GrnRect, GrnDot, RdDoT, GrnTxtD, GrnString, GRNPOLY, GRNERASE
C00009 00003	INTERNAL SIMPLE PROCEDURE GrnLine(INTEGER X1,Y1,X2,Y2 INTEGER bitmask(1))
C00011 00004	INTERNAL SIMPLE PROCEDURE GrnRect(INTEGER X1,Y1,X2,Y2 INTEGER bitmask(1))
C00013 00005	INTERNAL SIMPLE PROCEDURE GrnDot(REAL X,Y INTEGER bitmask)
C00015 00006	INTERNAL SIMPLE PROCEDURE GrnTxtD(REFERENCE INTEGER x,y INTEGER ARRAY chars 
C00017 00007	INTERNAL SIMPLE PROCEDURE GrnString(INTEGER x,y STRING S BOOLEAN DOUBLE(FALSE))
C00019 00008	INTERNAL SIMPLE PROCEDURE GRNERASE(INTEGER CHAN, SUBCHAN('377))
C00020 00009	INTERNAL PROCEDURE GRNPOLY(INTEGER ARRAY pts INTEGER Npts, VALUE('377))
C00034 ENDMK
C⊗;
ENTRY GrnLine, GrnRect, GrnDot, RdDoT, GrnTxtD, GrnString, GRNPOLY, GRNERASE;

BEGIN "GRNFUN"

DEFINE ! = "COMMENT",
       UPTO = "STEP 1 UNTIL";
! Require definitions;
REQUIRE "PIXHDR.SAI[HDR,HE]" SOURCE_FILE;
REQUIRE "GRNDEF[hdr,he]" SOURCE_FILE;
REQUIRE "ELFHDR.SAI[hdr,he]" SOURCE_FILE;
REQUIRE "GRNHDR.SAI[hdr,he]" SOURCE_FILE;

INTERNAL SIMPLE PROCEDURE GrnLine(INTEGER X1,Y1,X2,Y2; INTEGER bitmask(1));
  ! This Procedure draws a vector on the Grinnell
		between the pixels (x1,y1) and (x2,y2);
  BEGIN "GrnLine"

	GrnIns(LSM LOR '377); 		! set first to erase line;
	GrnIns(LWM LOR BITV LOR BITB);	! Vector drawing, dark line;
	GrnIns(LUM LOR L1 LOR E1); 	! Set updating;

	GrnIns(LLA LOR (y1 LAND '777));   	! Load line reg A with line number;
	GrnIns(LEA LOR (x1 LAND '777));	 	! Load element reg A w/element #;
	GrnIns(LLB LOR ((y2-y1) LAND '777)); 	! Vectors are drawn between (Ea,La);
	GrnIns(LEB LOR ((x2-x1) LAND '777) LOR WBIT);   ! and (Ea+Eb,La+Lb);

	GrnIns(LSM LOR bitmask); 	! Enable the bits to be written;
	GrnIns(LWM LOR BITV);		! Rectilinear drawing, light line now;
	GrnIns(LLA LOR (y1 LAND '777));   	! Load line reg A with line number;
	GrnIns(LEA LOR (x1 LAND '777));	 	! Load element reg A w/element #;
	GrnIns(LLB LOR ((y2-y1) LAND '777)); 	! Vectors are drawn between (Ea,La);
	GrnIns(LEB LOR ((x2-x1) LAND '777) LOR WBIT);   ! and (Ea+Eb,La+Lb);

  END "GrnLine";

INTERNAL SIMPLE PROCEDURE GrnRect(INTEGER X1,Y1,X2,Y2; INTEGER bitmask(1));
  ! This Procedure draws a vector on the Grinnell
		between the pixels (x1,y1) and (x2,y2);
  BEGIN "GrnLine"

	GrnIns(LSM LOR '377); 		! set first to erase line;
	GrnIns(LWM LOR BITB);	! Vector drawing, dark line;
	GrnIns(LUM LOR L1 LOR E1); 	! Set updating;

	GrnIns(LLA LOR (y1 LAND '777));   	! Load line reg A with line number;
	GrnIns(LEA LOR (x1 LAND '777));	 	! Load element reg A w/element #;
	GrnIns(LLB LOR ((y2-y1) LAND '777)); 	! Vectors are drawn between (Ea,La);
	GrnIns(LEB LOR ((x2-x1) LAND '777) LOR WBIT);   ! and (Ea+Eb,La+Lb);

	GrnIns(LSM LOR bitmask); 	! Enable the bits to be written;
	GrnIns(LWM);			! Rectilinear drawing, light line now;
	GrnIns(LLA LOR (y1 LAND '777));   	! Load line reg A with line number;
	GrnIns(LEA LOR (x1 LAND '777));	 	! Load element reg A w/element #;
	GrnIns(LLB LOR ((y2-y1) LAND '777)); 	! Vectors are drawn between (Ea,La);
	GrnIns(LEB LOR ((x2-x1) LAND '777) LOR WBIT);   ! and (Ea+Eb,La+Lb);

  END "GrnLine";
INTERNAL SIMPLE PROCEDURE GrnDot(REAL X,Y; INTEGER bitmask);
  ! GrnDot turns on the pixels corresponding to the pixel coordinates x,y;
  BEGIN "GrnDot"
    INTEGER line, element;

      line ← y;      ! Get screen coord.;
      element ← x;

!     GrnIns(LWM LOR BITZ);       ! make it write byte;
      GrnIns(LEA LOR element);    ! 8 bit graphics words are written left to right;
      GrnIns(LLA LOR line);       ! starting at (Ea, La);
      GrnIns(WID LOR bitmask);    ! Write graphic data = 10000000 in binary;

  END "GrnDot";

INTERNAL SIMPLE INTEGER PROCEDURE RDDOT(INTEGER X, Y);
  BEGIN
    INTEGER int;
    GrnIns(LEA LOR X);
    GrnIns(LLA LOR Y);
    GrnIns(SPD LOR READBACK);	! Set read mode;
    GRNIN(LOCATION(int),1);
    RETURN(int);
  END;
INTERNAL SIMPLE PROCEDURE GrnTxtD(REFERENCE INTEGER x,y; INTEGER ARRAY chars; 
	INTEGER Nchars);
  ! GrnTxt will output the text represented by the ASCII code in the array chars;
  ! starting at location (x,y);

  BEGIN "GrnTxt"
    DEFINE charwidth = 7;
    INTEGER ln, element, i;

    ln ← y;			! Convert to screen coordinates;
    element ← x;

    GrnIns(LUM LOR E1);		! Load update mode to be Ea ← Ea+Eb, La ← La;
    GrnIns(LEB LOR charwidth);  ! LD Eb with char width;
    GrnIns(LEA LOR element);	! Set up start location for text;
    GrnIns(LLA LOR ln);

    FOR i ← 1 step 1 UNTIL Nchars DO	! Now output the text;
  	GrnIns(WAC LOR chars[i]);

    x ← x + Nchars*charwidth; 

  END "GrnTxt";

INTERNAL SIMPLE PROCEDURE GrnString(INTEGER x,y; STRING S; BOOLEAN DOUBLE(FALSE));

  BEGIN "GrnString"
    INTEGER CHARWIDTH;
    INTEGER ln, element, i;

    ln ← y;			! Convert to screen coordinates;
    element ← x;

    IF DOUBLE THEN
	BEGIN
	    GRNINS(LWM LOR BITH LOR BITW);
	    CHARWIDTH ← 14
	END
    ELSE
	CHARWIDTH ← 7;

    GrnIns(LUM LOR E1);		! Load update mode to be Ea ← Ea+Eb, La ← La;
    GrnIns(LEB LOR charwidth);  ! LD Eb with char width;
    GrnIns(LEA LOR element);	! Set up start location for text;
    GrnIns(LLA LOR ln);

    FOR i ← 1 step 1 UNTIL LENGTH(S) DO	! Now output the text;
  	GrnIns(WAC LOR S[i FOR 1]);

  END "GrnString";

INTERNAL SIMPLE PROCEDURE GRNERASE(INTEGER CHAN, SUBCHAN('377));
  BEGIN "GRNERASE"
	GRNINS(LDC LOR (1 LSH CHAN));
	GRNINS(LSM LOR SUBCHAN);
	GRNINS(ERS);
  END "GRNERASE";
INTERNAL PROCEDURE GRNPOLY(INTEGER ARRAY pts; INTEGER Npts, VALUE('377));
BEGIN "GRNPOLY"
COMMENT ************** GRNPOLY  OVERVIEW ***************************************
	The following routine to fill arbitrary n sided polygons is modeled
  	after an algorithm described in Newman and Sproul's "Principals of 
	Interactive Computer Graphics", McGraw Hill, 2nd Ed. 
	The algorithm first builds a bucket of edges sorted first by Y coordinate
	and then into a list by the X coordinate. Each edge is represented by
	an x value, dx the amount by which x changes from each scanline, and dy
	the number of scanlines that edge intersects (the diffence between the 
	y values of the endpoints). Also the edge record contains a pointer to 
	the next edge in the list. So after the data structure is initialized
	with the edges;

  RECORD!CLASS Edge(INTEGER ydiff; REAL xcoord, slope; RECORD!POINTER(Edge) nxt);

! The following definitions make record field access less cunbersome;
  DEFINE  X(PTR)  = "Edge:xcoord[ptr]",	  
	  dx(ptr) = "Edge:slope[ptr]",
	  dy(ptr) = "Edge:ydiff[ptr]",
	  nxtedge(ptr) = "Edge:nxt[ptr]"; 

PROCEDURE InsertbyX(REFERENCE RECORD!POINTER (Edge) dest; RECORD!POINTER(Edge) src);
 BEGIN "InsertbyX"
   ! This routine will insert the sorted src list into the sorted dest list
     by the x field of the record;

   RECORD!POINTER (Edge) prevedge, curedge;
   BOOLEAN done;

  
   IF dest = NULL!RECORD THEN dest ← src
   ELSE BEGIN
       curedge ← dest;		! Start off pointing at the first edge in dest list;
       prevedge ← dest;
       IF x(dest) > x(src) AND src ≠ NULL!RECORD THEN BEGIN  
	    dest ← src;
	    src ← nxtedge(src);
	    nxtedge(dest) ← prevedge;
	    curedge ← nxtedge(dest);
	    prevedge ← dest;
       END;

       done ← false;

       WHILE src ≠ NULL!RECORD AND NOT done DO
	 BEGIN 
	    IF curedge = NULL!RECORD THEN BEGIN 
		! Print("adding src to dest at end of list",crlf);
		nxtedge(prevedge) ← src;
		done ← TRUE;
	    END
	    ELSE
		IF x(curedge) ≤ x(src) THEN BEGIN
		    prevedge ← curedge;
		    curedge ← nxtedge(curedge);
		END
		ELSE BEGIN
		    ! Print("adding src to dest in middle of list",crlf);
		    nxtedge(prevedge) ← src;
		    prevedge ← src;
		    src ← nxtedge(src);
		    nxtedge(prevedge) ← curedge;
		END;
    	  END;
    END;
    ! Print("In insertbyx ",crlf);
    ! Printedge(dest);
END "InsertbyX";

PROCEDURE KeepSortbyX(REFERENCE RECORD!POINTER (Edge) edgelist);
  BEGIN "KeepSort"
    RECORD!POINTER (Edge) prevedge, curedge;

    prevedge ← curedge ← edgelist;
    IF curedge ≠ NULL!RECORD THEN
	WHILE nxtedge(curedge) ≠ NULL!RECORD DO 
	    BEGIN
	       IF x(curedge) ≤ x(nxtedge(curedge)) THEN BEGIN
		    prevedge ← curedge;
		    curedge  ← nxtedge(curedge);
		END
		ELSE BEGIN
		    IF curedge = edgelist THEN BEGIN
			prevedge ← edgelist ← nxtedge(curedge);
			nxtedge(curedge) ← NULL!RECORD;
			Insertbyx(edgelist,curedge);
			curedge ← edgelist;
		    END
		    ELSE BEGIN
			nxtedge(prevedge) ← nxtedge(curedge);
			nxtedge(curedge) ← NULL!RECORD;
			InsertbyX(edgelist, curedge);
			curedge ← nxtedge(prevedge);
		    END;
		END; 
	     END;
  END "KeepSort";
PROCEDURE DrawPoly(INTEGER ARRAY pts; INTEGER npts, miny, maxy);
  BEGIN "DrawPoly"
  ! This routine determines and draws the scanlines to fill in the polygon;
  
    RECORD!POINTER (Edge) ARRAY ybucket [miny:maxy];	
    RECORD!POINTER (Edge) curline, newedge, Redge, Ledge, prevedge, curedge;
    INTEGER n, prevn, maxpt, scanln, deltay;

! **************** VARIABLES *****************************************************
   PARAMETERS:
	pts		Array with  x,y in screen coordinates of consecutive 
			vertexes of the polygon
	npts		Number of edges in the polygon
	miny		Minimum y value in pts
	maxy 		Maximum y value in pts
  
   LOCAL VARIABLES:
	ybucket  	Pointers to the Edge list for each scanline
	curline		Current edge list scanline is filled between pairs of edges
			in this list
	newedge		Pointer to newedge to be put into ybucket
	Redge		Points to right edge of pair when drawing a scanline
	Ledge		Points to left edge of above mentioned pair
	prevedge	Temporay pointer to keep track of the previous edge in the
			list
	curedge		Temporay pointer for current edge in list

	n		array index of npts
	prevn 		n - 1
	maxpt		Index of the endpoint with the maximum y value
	scanln		Current scanline of display
	deltay		Difference between y values between endpoints of an edge
  ********************************************************************************;


  ! Initialization of Data Structure;
  ! Edges are sorted by the maximum y value into a bucket and then in order of ;
  ! creasing X value.;

    prevn ← npts;
    n ← 1;
    WHILE N ≤ npts DO 
        BEGIN
	deltay ← pts[n,2] - pts[prevn,2];
	   IF deltay  ≠ 0 THEN		! Horisontal edges (dy=0] are not included;
		BEGIN
		 ! Initialize newedge;
 		   newedge ← NEW!RECORD(Edge);		
		   dy(newedge) ← ABS(deltay);
		   maxpt ← n;				! Find index of larger y;
		   IF deltay < 0 THEN maxpt ← prevn;

		   x(newedge) ← pts[maxpt,1];	
		   dx(newedge) ← (pts[prevn,1] - pts[n,1])/deltay;

		 ! Insert edge into bucket by the larger y value and by then by x;
		   InsertbyX(ybucket[pts[maxpt,2]],newedge);	
		END;
	   prevn ← n;  n ← n + 1;	! point to the next edge;
	END;


      ! Now that the data structure is initialized the output of the individual
	scanlines can proceed.;

      ! To get things started the topmost scanline is drawn;
	curline ← Redge ← ybucket[maxy];
	WHILE Redge ≠ NULL!RECORD DO BEGIN
	    Ledge ← nxtedge(Redge);
	    IF (maxy≤511) and (maxy≥0) THEN
	      GRNLine(((0 max x(Redge)) min 511),maxy,
			((0 max x(Ledge)) min 511), maxy,VALUE);
	    Redge ← nxtedge(Ledge);
	End;

      ! Now the remaining lines except the last are updated and drawn;
 	FOR scanln ← maxy - 1  STEP -1 UNTIL  miny + 1 DO BEGIN
	  ! Update current edge list;
	    curedge ← prevedge ← curline;
	    WHILE curedge ≠ NULL!RECORD DO BEGIN
	      ! first delete any edges that are finished dy = 0;
		IF (dy(curedge) ← dy(curedge) -1) = 0 THEN
		    IF curedge = curline THEN 
			prevedge ← curline ← curedge ← nxtedge(curedge)
		    ELSE nxtedge(prevedge) ← curedge ← nxtedge(curedge)
		ELSE BEGIN
		  ! change x for the nxt line;
		    x(curedge) ← x(curedge) + dx(curedge);
		    prevedge ← curedge;
		    curedge ← nxtedge(curedge);
		END;
	    END;

	  ! If any edges cross the current edge list must be resorted by x;
	    KeepSortbyX(curline);

	  ! Insert any new edges into current edge list;
	    IF ybucket[scanln] ≠ NULL!RECORD THEN
		    InsertbyX(curline,ybucket[scanln]);

	  ! Print current scanline;
	    Redge ← curline;
	    WHILE Redge ≠ NULL!RECORD DO BEGIN
		Ledge ← nxtedge(Redge);
		IF (scanln≤511) and (scanln≥0) THEN
		  GRNLine(((0 max x(Redge)) min 511),scanln,
			((0 max x(Ledge)) min 511), scanln,VALUE);
		Redge ← nxtedge(Ledge);
	    End;
	END;

      ! Update last line without deleteing edges with dy = 0;
	curedge ← curline;
	WHILE curedge ≠ NULL!RECORD DO BEGIN
	    x(curedge) ← x(curedge) + dx(curedge);
	    curedge ← nxtedge(curedge);
	END;
	KeepSortbyX(curline);

      ! Draw last line;
	Redge ← curline;
	WHILE Redge ≠ NULL!RECORD DO BEGIN
	    Ledge ← nxtedge(Redge);
	    ! Print("current edge",crlf);
	    ! PrintEdge(curline);
	    IF (miny≤511) and (miny≥0) THEN
	      GRNLine(((0 max x(Redge)) min 511),miny,
		    ((0 max x(Ledge)) min 511), miny,VALUE);
	    Redge ← nxtedge(Ledge);
	End;
  END "DrawPoly";
		   
  BEGIN "FillPolygon"
  ! this block finds the maximum y value of all vertexes and calls Drawpoly;
   INTEGER i, yi, miny, maxy, xi, minx, maxx;
   
   ! Find the maximum and minimum y values;
   maxy ← miny ← pts[1,2];
   FOR i ← 2 UPTO npts DO
      BEGIN
	yi ← pts[i,2];
	IF yi > maxy THEN maxy ← yi
	ELSE IF yi < miny THEN miny ← yi;
      END;
   
   IF miny = maxy THEN BEGIN	    ! deginerate case Polygon is a horizontal line;
       maxx ← minx ← pts[1,1];
       FOR i ← 2 UPTO npts DO
	  BEGIN
	    xi ← pts[i,1];
	    IF xi > maxx THEN maxx ← xi
	    ELSE IF xi < minx THEN minx ← xi;
	  END;
	IF (miny≤511) and (miny≥0) THEN
	  GRNLine(((0 max minx) min 511),miny,
		((0 max maxx) min 511), miny,VALUE);
    END
    ELSE DrawPoly(pts, npts, miny, maxy);   ! Draw filled in polygon;
  END "FillPolygon";
END "GRNPOLY";
END "GRNFUN";